home *** CD-ROM | disk | FTP | other *** search
- ;----------------------------------------------------------------------
- ; SPECTRUM is a memory resident utility that allows the EGA palette
- ; registers to be mapped to any of the 64 possible colors provided by
- ; the EGA. The interface uses the cursor pad keys to select and change
- ; the colors. RIGHT/LEFT arrow selects the color to be mapped. UP/DOWN
- ; arrow changes the 2/3 intensity color bits RGB. PGUP/PGDN changes the
- ; 1/3 intensity color bits rgb. Home restores the default color mapping.
- ; ESC exits and restores the colors at entry. END exits and makes the
- ; current screen colors permanent. SPECTRUM is reasonably colorfast, but
- ; if colors are lost, pop up and exit SPECTRUM to restore the colors.
- ;======================================================================
- CSEG SEGMENT PARA PUBLIC 'CODE'
- ORG 100H ;COM file format
-
- ASSUME CS:CSEG,DS:CSEG,ES:CSEG,SS:CSEG
- ;----------------------------------------------------------------------
- ; Equates - substituted literally when assembled.
- ;----------------------------------------------------------------------
- CR EQU 0DH ;HEX for carriage return
- LF EQU 0AH ; and line feed
- ;CTRL-TILDE
- HOTKEY EQU 29H ;SCAN code for tilde
- SHIFT_MASK EQU 04H ;Mask to pick out 'shifts'
- ;1000 = ALT 0100 = CTRL
- ;0010 = L SHIFT 0001 = R SHIFT
-
- NROW EQU 10 ;Number of rows in the window
- NCOL EQU 80 ;Number of cols in the window
- BOX_ROW EQU 10 ;Top row of window on screen
- BOX_COL EQU 0 ;Left col of window on screen
- BW_ATTR EQU 70H ;Monochrome window
- CO_ATTR EQU 17H ;Color window
-
- ;----------------------------------------------------------------------
- ; COM file entry point is at 100h
- ;----------------------------------------------------------------------
- ENTPT: JMP INITIALIZE ;Perform initialization
-
- COPYRIGHT DB "SPECTRUM 1.0 (c) 1987, Ziff-Davis Publishing Corp."
- DB CR,LF,"$",01AH
- AUTHOR DB "Programmed by Robert L. Hummel"
- ;----------------------------------------------------------------------
- ; Data used by INT_9 procedure. Other data precedes other procedures.
- ;----------------------------------------------------------------------
- OLD_INT_9 DD 0 ;Storage for old vectors
- OLD_INT_10 DD 0
- OLD_INT_21 DD 0
- DOS_FLAG DD 0 ;Address of dos critical flag
- INFO_PTR DD 00000487H ;0:487H
-
- ACTIVE DB 0 ;Inside pop-up
- LO_FN_FLAG DB 0 ;When inside Int 21h
-
- DISPLAY_PAGE DB 0 ;Used by screen save
- CURSOR_POS DW 0 ; to restore info
- ATTRIBUTE DB 0 ;Window color
-
- ;======================================================================
- ; New Interrupt 9 routine. Invoked each key-press.
- ; Test to see if our key combination has been typed.
- ;----------------------------------------------------------------------
- INT_9 PROC FAR
- ASSUME CS:CSEG, DS:NOTHING, ES:NOTHING, SS:NOTHING
- ;(Flags saved by INT)
- STI ;Allow interrupts
- PUSH AX ;Save used register
-
- IN AL,60H ;Get key scan code
- CMP AL,HOTKEY ;Check if hot-key
- JNE PROCESS_KEY ;If not, continue on.
-
- MOV AH,2 ;Get shift status fn
- INT 16H ;Thru BIOS
-
- AND AL,0FH ;Test only for 'shift' keys
- CMP AL,SHIFT_MASK ;If they match our combination
- JE OUR_KEY ;then is our signal
- PROCESS_KEY:
- POP AX ;Restore register
- JMP DWORD PTR CS:OLD_INT_9 ;Process key as normal
- OUR_KEY:
- ;----------------------------------------------------------------------
- ; Reset the keyboard interrupt controller (forget the key stroke)
- ;----------------------------------------------------------------------
- IN AL,61H ;These instructions reset
- MOV AH,AL ; the keyboard.
- OR AL,80H
- OUT 61H,AL
- MOV AL,AH
- JMP SHORT $+2 ;I/O delay for fast AT's
- OUT 61H,AL
- CLI ;Disable interrupts and
- MOV AL,20H ;reset the int controller
- OUT 20H,AL
- STI ;Allow interrupts
- ;----------------------------------------------------------------------
- ; If SPECTRUM is already active, or DOS is busy, simply return.
- ;----------------------------------------------------------------------
- CMP CS:ACTIVE,0 ;If already active
- JNE RETURN_A ; can't call again
-
- PUSH DS ;Save used registers
- PUSH BX
- LDS BX,CS:DOS_FLAG ;If DOS critical flag is not
- CMP BYTE PTR [BX],0 ; busy (= 0)
- JE INVOKE ;We can pop up
-
- CMP CS:LO_FN_FLAG,0 ;If busy from low function
- JNE INVOKE ; of Int 21h, go pop up
- RETURN_B:
- POP BX ;Restore other registers
- POP DS
- RETURN_A:
- POP AX ;Restore register
- IRET ;Go back where we came from
- INVOKE:
- ;----------------------------------------------------------------------
- ; Test, and pop up, only if the EGA is the active monitor.
- ;----------------------------------------------------------------------
- LDS BX,CS:INFO_PTR ;Get address of info byte
- LDS BX,[BX] ; and then byte itself
- TEST BL,08H ;Bit = 0 if EGA is active
- JNZ RETURN_B ; else don't pop up
-
- ;-----------------------------------------------------------------------------
- ; Check for valid text video mode. Set colors for BW or color modes.
- ;-----------------------------------------------------------------------------
- MOV ATTRIBUTE,CO_ATTR ;Assume color window
- MOV AH,0FH ;Get current video mode fn
- INT 10H ; Thru BIOS
- MOV DISPLAY_PAGE,BH ;Save current page
-
- CMP AL,3 ;One of the color text modes?
- JBE MODE_OK ; thats ok
- MOV ATTRIBUTE,BW_ATTR ;Assume mono window
- CMP AL,7 ;MONO 80x25 is valid
- JNE RETURN_B ; else don't pop up
- MODE_OK:
- ;-----------------------------------------------------------------------------
- ; If here, routine becomes active, save all other used registers.
- ;-----------------------------------------------------------------------------
- INC CS:ACTIVE ;Set flag to prevent re-entry
-
- PUSH CX ;Save all registers for return
- PUSH DX
- PUSH DI
- PUSH SI
- PUSH ES
- PUSH BP
-
- PUSH CS ;Put our CS into these regs
- POP DS ;So we can find our data
- PUSH CS
- POP ES ;And our string moves
- ASSUME DS:CSEG,ES:CSEG ;Tell the Assembler
- ;-----------------------------------------------------------------------------
- ; Save the details of the current screen for later restoration.
- ;-----------------------------------------------------------------------------
- MOV AH,3 ;Get cursor position fn
- INT 10H ;Thru BIOS
- MOV CURSOR_POS,DX ;Save position
-
- ;-----------------------------------------------------------------------------
- ; Save section of screen we will be writing over.
- ;-----------------------------------------------------------------------------
- MOV DI,OFFSET SCREEN_BUF ;Destination for save
- MOV SI,0FFFFH ;Switch tells proc to save
- CALL SCREEN
-
- CALL CLR_BOX ;Clear box & draw border
- CALL SPECTRUM ;Do all color mapping
-
- ;-----------------------------------------------------------------------------
- ; Restore the screen to original state.
- ;-----------------------------------------------------------------------------
- MOV SI,OFFSET SCREEN_BUF ;Address of saved screen
- CALL SCREEN ;Restore
-
- MOV AH,2 ;Set Cursor position fn
- MOV DX,CURSOR_POS ;Restore old cursor position
- INT 10H ;Thru BIOS
-
- MOV ACTIVE,0 ;Turn off active flag
-
- POP BP ;Restore all used registers
- POP ES
- POP SI
- POP DI
- POP DX
- POP CX
- POP BX
- POP DS
- POP AX
-
- IRET ;Interrupt gets IRET
- INT_9 ENDP
-
- ;======================================================================
- ; Spectrum data & equates.
- ;----------------------------------------------------------------------
- RT_ARROW EQU 4DH ;Extended ASCII for keys
- LT_ARROW EQU 4BH
- UP_ARROW EQU 48H
- DN_ARROW EQU 50H
- PAGE_UP EQU 49H
- PAGE_DN EQU 51H
- END_KEY EQU 4FH
- HOME EQU 47H
- ESCAPE EQU 1BH ;ASCII for escape
-
- DEFAULT_COLORS DB 00H,01H,02H,03H,04H,05H,14H,07H ;Restore with home
- DB 38H,39H,3AH,3BH,3CH,3DH,3EH,3FH
-
- OLD_COLORS DB 00H,01H,02H,03H,04H,05H,14H,07H ;May be set by loader
- DB 38H,39H,3AH,3BH,3CH,3DH,3EH,3FH
-
- BOX_PTR DB 0 ;Arrow location counter
-
- ;----------------------------------------------------------------------
- ; Display and set the colors for the EGA card by re-mapping the palette
- ; registers. Works best with EGD, but ok with CGD or MD.
- ;----------------------------------------------------------------------
- SPECTRUM PROC NEAR
- ASSUME CS:CSEG, DS:CSEG, ES:CSEG
-
- MOV BOX_PTR,0 ;Point to 1st box
- CALL SP_3 ;Copy last known colors
- ;to scratch copy & set regs
- ;----------------------------------------------------------------------
- ;Set the pointer to the first box and listen for the required keystrokes
- ; > move right to next box < move left to previous box
- ; ^ increment rgb signal v decrement rgb signal
- ; pgup increment RGB signal pgdn decrement RGB signal
- ; ESC abort changes END save changes
- ; HOME load default colors
- ;----------------------------------------------------------------------
- SP_1:
- MOV AH,2 ;Position cursor fn
- MOV DH,BOX_ROW+5 ;Row
- MOV DL,BOX_PTR ;Column
- SHL DL,1 ; times 4
- SHL DL,1
- ADD DL,9 ; plus offset
- INT 10H ;Thru BIOS
-
- MOV AX,0E18H ;Write TTY, arrow char
- INT 10H ;Thru BIOS
- MOV AX,0E08H ;Backspace under it
- INT 10H ;THRU BIOS
- SP_2:
- XOR AH,AH ;Wait for keystroke in AL
- INT 16H ;Thru BIOS
-
- CMP AL,ESCAPE ;If ESCAPE character, leave
- JNE CMP_0A
- SP_3:
- MOV SI,OFFSET OLD_COLORS ;Copy old colors
- MOV DI,OFFSET NEW_COLORS ; to scratch copy
- SP_4:
- MOV CX,16 ;Bytes to move
- REP MOVSB ; move 'em
- CALL COLOR_BARS ;Set palette registers
- RET ;Return to calling procedure
- CMP_0A:
- XOR AL,AL ;If not extended ASCII
- JNZ SP_2 ; ignore it
-
- CMP AH,END_KEY ;END key means
- JNE CMP_0B
- MOV SI,OFFSET NEW_COLORS ;New colors become
- MOV DI,OFFSET OLD_COLORS ; permanent
- JMP SP_4
- CMP_0B:
- CMP AH,HOME ;HOME means
- JNE CMP_0C
- MOV SI,OFFSET DEFAULT_COLORS ;Reset to power-up colors
- MOV DI,OFFSET NEW_COLORS ; in scratch copy
- CALL SP_4 ;Change the registers
- JMP SP_1 ;Go wait for more keys
- CMP_0C:
- CMP AH,RT_ARROW ;Right arrow means
- JNE CMP_1
- INC BOX_PTR ; move to next box
- CMP_0:
- MOV AX,0E20H ;Write space over arrow
- INT 10H ;Thru BIOS
- AND BOX_PTR,15 ;Modulo 16 arithmetic
- JMP SP_1 ;Redraw arrow
- CMP_1:
- CMP AH,LT_ARROW ;Previous box
- JNE CMP_2
- DEC BOX_PTR
- JMP CMP_0 ;Adjust pointer
- ;----------------------------------------------------------------------
- ; Decode the palette value in case we need it.
- ;----------------------------------------------------------------------
- CMP_2:
- XOR BH,BH ;What register are we
- MOV BL,BOX_PTR ; pointing to?
- MOV CL,BYTE PTR NEW_COLORS[BX] ;Get palette value
- MOV CH,CL ;Duplicate
- AND CX,3807H ;CH=rgb, CL=RGB
-
- CMP AH,UP_ARROW
- JNE CMP_3
- INC CL ;Next RGB color
- CMP_2A:
- AND CL,7 ;7 = 00000111B
- JMP SHORT COMBINE
- CMP_3:
- CMP AH,DN_ARROW
- JNE CMP_4
- DEC CL ;Previous RGB color
- JMP CMP_2A
- CMP_4:
- CMP AH,PAGE_UP
- JNE CMP_5
- ADD CH,8 ;next rgb color
- CMP_4A:
- AND CH,38H ;38H = 00111000b
- JMP SHORT COMBINE
- CMP_5:
- CMP AH,PAGE_DN
- JNE CMP_6
- ADD CH,38H ;Previous rgb color
- JMP CMP_4A
- COMBINE:
- OR CL,CH ;Combine CL & CH
- MOV BYTE PTR NEW_COLORS[BX],CL ;Update color table
- CALL COLOR_BARS ; and palette registers
- CMP_6:
- JMP SP_1 ;Wait for next keystroke
- SPECTRUM ENDP
-
- ;======================================================================
- ; COLOR_BARS calls the EGA BIOS to map the attributes 0 thru 15 to the
- ; values in NEW_COLORS using the palette registers. To simplify use
- ; of the utility, the colors are labeled by a two digit number. The
- ; first digit is the decimal equivalent of the three major colors RGB.
- ; The second digit is rgb similarly. Finally, two rows of blocks of the
- ; color are displayed on screen.
- ; This routine depends heavily on values remaining in registers
- ; after BIOS calls. Pay attention when modifying.
- ; No registers are preserved.
- ;----------------------------------------------------------------------
- COLOR_BARS PROC NEAR
-
- CLD ;String moves forward
- MOV SI,OFFSET NEW_COLORS ;Set palette value to these
- MOV CX,16 ;Number of palette values
-
- MOV DL,BOX_COL+8 ;Col for numerical labels
- CLR_BAR1:
- PUSH CX ;Save counter
- MOV DH,BOX_ROW+6 ;Row for register # labels
-
- MOV AH,2 ;Position cursor function
- MOV BH,DISPLAY_PAGE
- INT 10H ;Thru BIOS
-
- MOV AL,16 ;Get palette #
- SUB AL,CL ; in AL
- PUSH AX ;Save palette #
- XOR AH,AH
- AAA ;Convert AL to decimal digits
- MOV CL,4 ;AH=10's, AL=1's
- SHL AH,CL
- OR AL,AH
- CALL HEX2CON ;Write to screen
-
- SUB DH,4 ;Row for value # labels
- MOV AH,2 ;Position cursor function
- INT 10H ;Thru BIOS
-
- LODSB ;Get value in AL
- POP BX ;Retrieve palette # in BL
- MOV BH,AL ;Attribute in BH
- MOV AX,1000H ;Set palette register fn
- INT 10H ;Thru BIOS
- ;----------------------------------------------------------------------
- ; Translate the hex color code into our (RGB)(rgb) numbering and display.
- ;----------------------------------------------------------------------
- MOV AL,BH ;Retrieve attribute
- MOV AH,AL ;rgbRGB in both AH & AL
- MOV CL,3 ;Shift count
- SHR AL,CL ;Put rgb in lower 4 bits
-
- AND AH,7 ;RGB bits
- MOV CL,4 ;Shift count
- SHL AH,CL ;Put RGB in upper 4 bits
- OR AL,AH ;Combine into single byte
- CALL HEX2CON ;Print AL to CON as 2 hex
- ; digits.
- MOV BH,DISPLAY_PAGE
- DEC DL ;Box begins 1 col to the left
- CALL DRAW_BAR ;Draw two rows
-
- ADD DL,5 ;Col for next label
- POP CX ;Restore counter
- LOOP CLR_BAR1
- RET
- COLOR_BARS ENDP
-
- ;======================================================================
- ; DRAW_BAR - Draw two rows of Block graphics char to show foreground
- ; color. AX,DX,CX destroyed.
- ;----------------------------------------------------------------------
- DRAW_BAR PROC NEAR
-
- CALL DRAW_1 ;Call ourself to repeat
- DRAW_1:
- INC DH ;Down one row
- MOV AH,2 ;Position cursor function
- INT 10H ;Thru BIOS
-
- MOV AX,09DBH ;Write repeated char/attr
- MOV CX,4 ; 4 copies of block
- INT 10H ; Thru BIOS
-
- RET ;Double duty
- DRAW_BAR ENDP
-
- ;======================================================================
- ; HEX2CON - print AL to CON as 2 hex digits.
- ; AX destroyed. Other registers preserved.
- ;-----------------------------------------------------------------------------
- HEX2CON PROC NEAR
-
- PUSH AX ;Save reg for second digit
-
- PUSH CX ;Save CX for use in shift
- MOV CL,4 ;Shift 4 bits
- SHR AL,CL ;Get high 4 bits in low end
- POP CX ;Restore register
-
- CALL H2C ;Print the digit in AL
- POP AX ;Get back original AL
- AND AL,0FH ;Take second digit
- H2C:
- ADD AL,90H ;Convert AL to ASCII
- DAA
- ADC AL,40H
- DAA
- MOV AH,0EH ;Write TTY
- INT 10H ; Thru BIOS
-
- RET ;Double duty
-
- HEX2CON ENDP
-
- ;======================================================================
- ; Perform the screen save/restore.
- ; SAVE: SI=FFFF, DI=buffer address
- ; RESTORE: SI=buffer address, DI=don't care
- ;----------------------------------------------------------------------
- SCREEN PROC NEAR
-
- CLD ;String moves forward
- MOV BH,DISPLAY_PAGE ;Just to be sure, reset page
-
- MOV CX,NROW ;Row loop
- MOV DH,BOX_ROW ;Init row pointer
- ROW_LOOP:
- PUSH CX ;Prepare for...
- MOV CX,NCOL ;...column loop
- MOV DL,BOX_COL ;Column Pointer
- COL_LOOP:
- PUSH CX ;Need for write-char fn
- MOV AH,2 ;Position cursor fn
- INT 10H ;Thru BIOS
-
- CMP SI,0FFFFH ;SI =FFFF if SAVE
- JE DO_SAVE
- ;RESTORE
- LODSW ;AX <- [SI]
- ;AH=ATTR AL=CHAR
- MOV BL,AH ;Put attribute where needed
- MOV AH,9 ;Write char fn
- MOV CX,01 ;Write one copy of char
- INT 10H ;Thru BIOS
- JMP SHORT DO_LOOP
- DO_SAVE:
- MOV AH,8 ;Get char & attribute fn
- INT 10H ;Thru BIOS
- STOSW ;[di+=2]=ax
- DO_LOOP:
- INC DL ;Next column
- POP CX ;Restore Counter
- LOOP COL_LOOP ;Close Inner loop
-
- POP CX ;Return to outer loop
- INC DH ;Next row
- LOOP ROW_LOOP ;Close Outer loop
- RET
-
- SCREEN ENDP
-
- ;======================================================================
- ; Clear a window (box) for our information on the screen.
- ; Add a border, name, and help line for a nice touch.
- ;----------------------------------------------------------------------
- BOX_MSG DB BOX_COL+2,BOX_ROW,0B5H,"SPECTRUM 1.0",0C6H,0
- BOX_CHARS DB 0C9H,0CDH,0BBH,0BAH,020H,0BAH,0C8H,0CDH,0BCH
- HELP_MSG DB BOX_COL+7,BOX_ROW+NROW-2
- DB "COLOR=",27,26," RGB=",24,25," rgb=PgUp/Dn "
- DB "Save=END Cancel=ESC Default=HOME",0
-
- CLR_BOX PROC NEAR
-
- MOV AX,0600H ;Scroll entire window fn
- MOV CH,BOX_ROW ;Upper row
- MOV CL,BOX_COL ;Left column
- MOV DH,BOX_ROW + NROW - 1 ;Bottom row
- MOV DL,BOX_COL + NCOL - 1 ;Right column
- MOV BH,ATTRIBUTE ;Window color
- INT 10H ;Thru BIOS
-
- MOV BH,DISPLAY_PAGE ;Use current page
- MOV SI,OFFSET BOX_CHARS ;Window border chars
- MOV DX,CX ;Cursor from last call
- MOV CX,NROW ;Number of rows to draw
- CB_1:
- PUSH CX ;Save counter
- MOV DL,BOX_COL ;Starting column
-
- MOV AH,2 ;Position cursor
- INT 10H ; Thru BIOS
-
- LODSB ;Get leftmost char
- MOV AH,0EH ;Write char TTY
- INT 10H ; Thru BIOS
-
- LODSB ;Get middle char
- MOV AH,0AH ;Write repeated char
- MOV CX,NCOL-2 ; This many times
- INT 10H ; Thru BIOS
-
- MOV AH,2 ;Position cursor
- MOV DL,BOX_COL + NCOL - 1 ;Col = righthand edge
- INT 10H ; Thru BIOS
-
- LODSB ;Get rightmost char
- MOV AH,0EH ;Write char TTY
- INT 10H ; Thru BIOS
-
- INC DH ;Next row
- POP CX ;Restore counter
-
- CMP CL,NROW ;If first row
- JE CB_2 ; choose next 3 chars
- CMP CL,2 ;If last row
- JE CB_2 ; choose next 3 chars
- SUB SI,3 ;Else, repeat these 3 again
- CB_2:
- LOOP CB_1 ;Row loop
-
- MOV SI,OFFSET BOX_MSG ;Write program name on box
- CALL WR_MESSAGE
- MOV SI,OFFSET HELP_MSG ;And help line on bottom
- CALL WR_MESSAGE
-
- RET
- CLR_BOX ENDP
-
- ;======================================================================
- ; Fill in the window information on screen. String format is col,row,text,0.
- ; DS:SI points to string.
- ;----------------------------------------------------------------------
- WR_MESSAGE PROC NEAR
-
- MOV BH,DISPLAY_PAGE ;This page
- LODSW ;Get intended position
- MOV DX,AX ; in DX
- MOV AH,2 ;Position cursor
- MSG_LOOP:
- INT 10H ;Thru BIOS
- MOV AH,0EH ;Write AL as TTY
- LODSB ;Get next char
- OR AL,AL ;If 0, end of string
- JNZ MSG_LOOP ; else, repeat
- RET
-
- WR_MESSAGE ENDP
-
- ;======================================================================
- ; Video Int 10h intercept. If mode is changed, reset colors.
- ; A font load changes modes internally and causes a reload.
- ;----------------------------------------------------------------------
- INT_10 PROC FAR
-
- OR AH,AH ;If video mode change
- JZ VIDEO_1 ; handle specially
- CMP AH,11H ;Or possible font load
- JZ VIDEO_1 ; (internal mode change)
- JMP DWORD PTR CS:OLD_INT_10 ;Resume old Video interrupt
- VIDEO_1:
- STI ;Allow interrupts
- PUSHF ;Simulate original interrupt
- CALL DWORD PTR CS:OLD_INT_10 ; and return here
-
- PUSH AX ;Save used registers
- PUSH BX
-
- MOV AH,0FH ;Get current video mode
- INT 10H ; Thru BIOS
- CMP AL,4 ;If color text modes
- JBE VIDEO_2
- CMP AL,7 ; or mono text mode
- JNE VIDEO_4
- VIDEO_2:
- PUSH CX ;Reset the palette regs
- PUSH SI
-
- MOV CX,16 ;# of registers to set
- MOV SI,OFFSET CS:OLD_COLORS+15 ;end of colors
- VIDEO_3:
- MOV AX,1000H ;Set palette register
- MOV BL,CL
- DEC BL ;Palette # in BL
- MOV BH,CS:[SI] ;Attribute in BH
- DEC SI ;Move pointer
- INT 10H ; Thru BIOS
- LOOP VIDEO_3
-
- POP SI ;Restore registers
- POP CX
- VIDEO_4:
- POP BX
- POP AX
- RET 2 ;Far return, pop flags
- ;to simulate IRET
- INT_10 ENDP
-
- ;======================================================================
- ; DOS Int 21h intercept. Set flag while uninterruptable
- ; The purpose of this procedure is to keep pop-up from taking control
- ; of the machine when doing so would cause a crash.
- ; (Function 0 changed to 4CH to avoid DOS problems with CS register.)
- ;----------------------------------------------------------------------
- INT_21 PROC FAR
-
- MOV CS:LO_FN_FLAG,0 ;Assume Not function 1-Ch
- CMP AH,0 ;If program is using DOS fn 0
- JNE CHECK
- MOV AH,4CH ;Change it to 4Ch
- GO_DIRECT:
- JMP DWORD PTR CS:OLD_INT_21 ;Jump to original routine
- CHECK:
- CMP AH,0CH ;DOS functions call under 0DH
- JA GO_DIRECT
-
- INC CS:LO_FN_FLAG ;Is low function
-
- PUSHF ;Simulate interrupt
- CALL DWORD PTR CS:OLD_INT_21 ; with FAR CALL
-
- MOV CS:LO_FN_FLAG,0 ;Turn off flag
- RET 2 ;Return to INT source and
- ;discard old flags
- INT_21 ENDP
-
- ;======================================================================
- ; Data here is allocated after the program loads into memory to save space
- ; in the COM file so the basic listing will be smaller.
- ; PC variable used to keep track of relative addresses.
- ;----------------------------------------------------------------------
- PC = $ ;Set imaginary counter
-
- SCREEN_BUF = PC ;DB NROW*NCOL*2 DUP(?)
- PC = PC + NROW * NCOL * 2
-
- NEW_COLORS = PC ;DB 16 DUP(?)
- PC = PC + 16
-
- LAST_BYTE = PC
-
- ;======================================================================
- ; Hook the necessary interrupts to avoid a collision.
- ; Terminate and Stay Resident (TSR).
- ;----------------------------------------------------------------------
- INITIALIZE PROC NEAR
- ASSUME CS:CSEG, DS:CSEG, ES:NOTHING, SS:CSEG
-
- MOV DX,OFFSET COPYRIGHT ;Say who we are as we leave
- MOV AH,9 ;Display string function
- INT 21H ;Thru DOS
-
- ;----------------------------------------------------------------------
- ; If command line parameters are present, load them into the registers
- ;----------------------------------------------------------------------
- CMP BYTE PTR DS:[80H],48 ;Must be 48 chars min to load
- JB NO_ARGS
-
- MOV SI,82H ;First parameter
- MOV DI,OFFSET OLD_COLORS ;Destination
- MOV CX,16
- PARM_LOOP:
- LODSW ;Get digits
- AND AX,0CFCFH ;Ascii to hex
- SHL AH,1
- SHL AH,1
- SHL AH,1
- OR AL,AH ;Combine in AH
- STOSB ;Put in OLD_COLORS
- INC SI ;Skip past delimiter
- MOV BH,AL ;Palette value in BH
- MOV AX,1000H ;Set palette fn
- MOV BL,16 ;Get palette number
- SUB BL,CL ; in BL
- INT 10H ;Thru BIOS
- LOOP PARM_LOOP
- NO_ARGS:
- ;----------------------------------------------------------------------
- ; Check if already loaded in memory. Don't load multiple copies.
- ;----------------------------------------------------------------------
- MOV WORD PTR [ENTPT+0],0 ;Modify to avoid false match
- MOV WORD PTR [ENTPT+2],0
-
- XOR BX,BX ;BX = segment to compare
- MOV AX,CS ;AX = our segment
- NEXT_PARA:
- INC BX ;Next paragraph
- CMP AX,BX ;If current paragraph...
- MOV ES,BX ;Set search segment
- JE END_SEARCH ;...stop
- MOV SI,OFFSET COPYRIGHT ;String to compare
- MOV DI,SI ;Offset is same
- MOV CX,16 ;Compare first 16 bytes
- REP CMPSB ;CMP DS:SI TO ES:DI
- OR CX,CX ;All matched?
- JNZ NEXT_PARA ;No.
- ;Found a copy in memory
- CMP BYTE PTR DS:[80H],48 ;If no parameters
- JL LEAVE_NO_TRACE ; do nothing
-
- MOV SI,OFFSET OLD_COLORS ;Load colors into memory
- MOV DI,SI
- MOV CX,16
- REP MOVSB ;From DS:SI to ES:DI
- LEAVE_NO_TRACE:
- MOV AX,4C01H ;Terminate with 'error'
- INT 21H ;Thru DOS
- END_SEARCH:
- ;----------------------------------------------------------------------
- ; Get a pointer to the DOS Critical Flag, a one-byte location in low memory
- ; that is set when DOS is in an uninterruptable state. Location is returned
- ; in ES:BX. This is undocumented, but works in DOS 2.0 - 3.21
- ;----------------------------------------------------------------------
- MOV AH,34H ;Get Interrupt Flag address
- INT 21H
-
- MOV WORD PTR DOS_FLAG[0],BX ;offset
- MOV WORD PTR DOS_FLAG[2],ES ;segment
- ;----------------------------------------------------------------------
- ; Hook the keyboard interrupt 9h for the hot-key detection routine.
- ; Hook DOS Interrupt 21h to set busy flag.
- ;----------------------------------------------------------------------
- PUSH DS ;Reset ES to point to same
- POP ES ; segment as DS
-
- MOV AL,9 ;Interrupt number
- MOV DI,OFFSET OLD_INT_9 ;Store vector here
- MOV DX,OFFSET INT_9 ;New interrupt procedure
- CALL SET_INT ;Make change
-
- MOV AL,10H
- MOV DI,OFFSET OLD_INT_10
- MOV DX,OFFSET INT_10
- CALL SET_INT
-
- MOV AL,21H
- MOV DI,OFFSET OLD_INT_21
- MOV DX,OFFSET INT_21
- CALL SET_INT
-
- ;----------------------------------------------------------------------
- ; Deallocate the copy of the environment loaded with the program.
- ; Establish memory residency and terminate.
- ;----------------------------------------------------------------------
- MOV AX,WORD PTR DS:[2CH] ;Address of environment
- MOV ES,AX ;In ES register
- MOV AH,49H ;Release allocated memory
- INT 21H ;Thru DOS
-
- MOV DX,(OFFSET LAST_BYTE - OFFSET CSEG + 15) SHR 4
- MOV AX,3100H ;Keep (TSR)
- INT 21H ;Thru DOS
-
- INITIALIZE ENDP
-
- ;======================================================================
- ; Get/Save/Set the interrupt vector. AL contains vector number.
- ; ES:DI points to DWORD destination for old address.
- ; DS:DX points to new interrupt address. AX destroyed.
- ;----------------------------------------------------------------------
- SET_INT PROC NEAR
- ASSUME CS:CSEG, DS:CSEG, ES:CSEG, SS:CSEG
-
- PUSH AX ;Save vector # in AL
- MOV AH,35H ;Get address function
- INT 21H ;Thru DOS
- MOV WORD PTR [DI+0],BX ;Save address in ES:DI
- MOV WORD PTR [DI+2],ES
- POP AX ;Get AL back
- MOV AH,25H ;Set new address to DS:DX
- INT 21H ;Thru DOS
- RET
-
- SET_INT ENDP
-
- CSEG ENDS
- END ENTPT